home *** CD-ROM | disk | FTP | other *** search
/ CU Amiga Super CD-ROM 11 / CU Amiga Magazine's Super CD-ROM 11 (1997)(EMAP Images)(GB)(Track 1 of 3)[!][issue 1997-06].iso / cucd / programming / oberonv4 / text / oberon2.report.text (.txt) < prev    next >
Oberon Text  |  1996-02-27  |  69KB  |  807 lines

  1. Syntax10.Scn.Fnt
  2. ParcElems
  3. Alloc
  4. Syntax14b.Scn.Fnt
  5. StyleElems
  6. Alloc
  7. Paragraph
  8. Syntax12b.Scn.Fnt
  9. Syntax10i.Scn.Fnt
  10. 2Syntax
  11. Paragraph
  12. Examples
  13. Paragraph
  14. 2Syntax
  15. Paragraph
  16. 2Syntax
  17. Paragraph
  18. Paragraph
  19. 2Syntax
  20. Paragraph
  21. Paragraph
  22. Paragraph
  23. Examples
  24. Paragraph
  25. Paragraph
  26. Programs
  27. Paragraph
  28. Syntax10b.Scn.Fnt
  29. Paragraph
  30. 2Syntax
  31. Paragraph
  32. 2Syntax
  33. Paragraph
  34. Programs
  35. Paragraph
  36. Programs
  37. Paragraph
  38. 2Syntax
  39. Paragraph
  40. Paragraph
  41. Paragraph
  42. Paragraph
  43. Paragraph
  44. Paragraph
  45. Paragraph
  46. Paragraph
  47. Examples
  48. Paragraph
  49. Examples
  50. Paragraph
  51. Programs
  52. Paragraph
  53. Paragraph
  54. Programs
  55. Paragraph
  56. Programs
  57. Paragraph
  58. Programs
  59. Paragraph
  60. Programs
  61. Paragraph
  62. Programs
  63. Paragraph
  64. Paragraph
  65. Paragraph
  66. Paragraph
  67. Paragraph
  68. Programs
  69. Paragraph
  70. Paragraph
  71. Programs
  72. Paragraph
  73. Paragraph
  74. Paragraph
  75. 2Syntax
  76. Paragraph
  77. Programs
  78. Paragraph
  79. Paragraph
  80. Paragraph
  81. Programs
  82. Paragraph
  83. Paragraph
  84. Programs
  85. Paragraph
  86. GraphicElems
  87. Alloc
  88. Elektra.Scn.Fnt
  89. Syntax10.Scn.Fnt
  90. (for garbage collector)
  91. Offsets of pointers in t^
  92. BaseTypes
  93. ProcTab
  94. of CenterNode
  95. type descriptor
  96. Rectangles
  97. CenterNode
  98. subnode
  99. width
  100. right
  101. Paragraph
  102. The Programming Language Oberon-2
  103. ssenb
  104. ck, N. Wirth
  105. Institut f
  106. r Computersysteme, ETH Z
  107. March 1995
  108. 1. Introduction
  109. Oberon-2 is a general-purpose programming language in the tradition of Pascal and Modula-2. Its most important features are block structure, modularity, separate compilation, static typing with strong type checking (also across module boundaries), and type extension with type-bound procedures.
  110.     Type extension makes Oberon-2 an object-oriented language. An object is a variable of an abstract data type consisting of private data (its state) and procedures that operate on this data. Abstract data types are declared as extensible records. Oberon-2 covers most terms of object-oriented languages by the established vocabulary of imperative languages in order to minimize the number of notions for similar concepts.
  111.     This report is not intended as a programmer's tutorial. It is intentionally kept concise. Its function is to serve as a reference for programmers, implementors, and manual writers. What remains unsaid is mostly left so intentionally, either because it can be derived from stated rules of the language, or because it would require to commit the definition when a general commitment appears as unwise.
  112.     Appendix A defines some terms that are used to express the type checking rules of Oberon-2. Where they appear in the text, they are written in italics to indicate their special meaning (e.g. the same type).
  113. 2. Syntax
  114. An extended Backus-Naur Formalism (EBNF) is used to describe the syntax of Oberon-2: Alternatives are separated by |. Brackets [ and ] denote optionality of the enclosed expression, and braces { and } denote its repetition (possibly 0 times). Non-terminal symbols start with an upper-case letter (e.g. Statement). Terminal symbols either start with a lower-case letter (e.g. ident), or are written all in upper-case letters (e.g. BEGIN), or are denoted by strings (e.g. ":=").
  115. 3. Vocabulary and Representation
  116. The representation of (terminal) symbols in terms of characters is defined using the ASCII set. Symbols are identifiers, numbers, strings, operators, and delimiters. The following lexical rules must be observed: Blanks and line breaks must not occur within symbols (except in comments, and blanks in strings). They are ignored unless they are essential to separate two consecutive symbols. Capital and lower-case letters are considered as distinct.
  117. 1. Identifiers are sequences of letters and digits. The first character must be a letter.
  118. ident = letter {letter | digit}.
  119. Examples:     x     Scan     Oberon2     GetSymbol     firstLetter
  120. 2. Numbers are (unsigned) integer or real constants. The type of an integer constant is the minimal type to which the constant value belongs (see 6.1). If the constant is specified with the suffix H, the representation is hexadecimal otherwise the representation is decimal.
  121.     A real number always contains a decimal point. Optionally it may also contain a decimal scale factor. The letter E (or D) means "times ten to the power of". A real number is of type REAL, unless it has a scale factor containing the letter D. In this case it is of type LONGREAL.
  122. number     = integer | real.
  123. integer     = digit {digit} | digit {hexDigit} "H".
  124. real     = digit {digit} "." {digit} [ScaleFactor].
  125. ScaleFactor     = ("E" | "D") ["+" | "-"] digit {digit}.
  126. hexDigit     = digit | "A" | "B" | "C" | "D" | "E" | "F".
  127. digit     = "0" | "1" | "2" | "3" | "4" | "5" | "6" | "7" | "8" | "9".
  128. Examples:
  129. 1991    INTEGER    1991
  130. 0DH     SHORTINT    13
  131. 12.3    REAL    12.3
  132. 4.567E8     REAL    456700000
  133. 0.57712566D-6     LONGREAL    0.00000057712566
  134. 3. Character constants are denoted by the ordinal number of the character in hexadecimal notation followed by the letter X.
  135. character  = digit {hexDigit} "X".
  136. 4. Strings are sequences of characters enclosed in single (') or double (") quote marks. The opening quote must be the same as the closing quote and must not occur within the string. The number of characters in a string is called its length. A string of length 1 can be used wherever a character constant is allowed and vice versa.
  137. string  = ' " ' {char} ' " ' | " ' " {char} " ' ".
  138. Examples:     "Oberon-2"     "Don't worry!"     "x"
  139. 5. Operators and delimiters are the special characters, character pairs, or reserved words listed below. The reserved words consist exclusively of capital letters and cannot be used as identifiers.
  140. +    :=    ARRAY    IMPORT    RETURN
  141. -    ^    BEGIN    IN    THEN
  142. *    =    BY    IS    TO
  143. /    #    CASE    LOOP    TYPE
  144. ~    <    CONST    MOD    UNTIL
  145. &    >    DIV    MODULE    VAR
  146. .    <=    DO    NIL    WHILE
  147. ,    >=    ELSE    OF    WITH
  148. ;    ..    ELSIF    OR
  149. |    :    END    POINTER
  150. (    )    EXIT    PROCEDURE
  151. [    ]    FOR    RECORD
  152. {    }    IF    REPEAT
  153. 6. Comments may be inserted between any two symbols in a program. They are arbitrary character sequences opened by the bracket (* and closed by *). Comments may be nested. They do not affect the meaning of a program.
  154. 4. Declarations and scope rules
  155. Every identifier occurring in a program must be introduced by a declaration, unless it is a predeclared identifier. Declarations also specify certain permanent properties of an object, such as whether it is a constant, a type, a variable, or a procedure. The identifier is then used to refer to the associated object. 
  156.     The scope of an object x extends textually from the point of its declaration to the end of the block (module, procedure, or record) to which the declaration belongs and hence to which the object is local. It excludes the scopes of equally named objects which are declared in nested blocks. The scope rules are:
  157.     1.  No identifier may denote more than one object within a given scope (i.e. no identifier may be declared twice in a 
  158.         block);
  159.     2.  An object may only be referenced within its scope;
  160.     3.  A type T of the form POINTER TO T1 (see 6.4) can be declared at a point where T1 is still unknown. The declaration 
  161.         of T1 must follow in the same block to which T is local;
  162.     4.  Identifiers denoting record fields (see 6.3) or type-bound procedures (see 10.2) are valid in record designators only.
  163. An identifier declared in a module block may be followed by an export mark (" * " or " - ") in its declaration to indicate that it is exported. An identifier x exported by a module M may be used in other modules, if they import M (see Ch.11). The identifier is then denoted as M.x in these modules and is called a qualified identifier. Identifiers marked with " - " in their declaration are read-only in importing modules.
  164. Qualident     = [ident "."] ident.
  165. IdentDef     = ident [" * " | " - "].
  166. The following identifiers are predeclared; their meaning is defined in the indicated sections:
  167. ABS    (10.3)    LEN    (10.3)
  168. ASH    (10.3)    LONG    (10.3)
  169. BOOLEAN    (6.1)    LONGINT    (6.1)
  170. CAP    (10.3)    LONGREAL    (6.1)
  171. CHAR    (6.1)    MAX    (10.3)
  172. CHR    (10.3)    MIN    (10.3)
  173. COPY    (10.3)    NEW    (10.3)
  174. DEC    (10.3)    ODD    (10.3)
  175. ENTIER    (10.3)    ORD    (10.3)
  176. EXCL    (10.3)    REAL    (6.1)
  177. FALSE    (6.1)    SET    (6.1)
  178. HALT    (10.3)    SHORT    (10.3)
  179. INC    (10.3)    SHORTINT    (6.1)
  180. INCL    (10.3)    SIZE    (10.3)
  181. INTEGER    (6.1)    TRUE    (6.1)
  182. 5. Constant declarations
  183. A constant declaration associates an identifier with a constant value.
  184. ConstantDeclaration     = IdentDef "=" ConstExpression.
  185. ConstExpression     = Expression.
  186. A constant expression is an expression that can be evaluated by a mere textual scan without actually executing the program. Its operands are constants (Ch.8) or predeclared functions (Ch.10.3) that can be evaluated at compile time. Examples of constant declarations are:
  187. N = 100
  188. limit = 2*N - 1
  189. fullSet = {MIN(SET) .. MAX(SET)}
  190. 6. Type declarations
  191. A data type determines the set of values which variables of that type may assume, and the operators that are applicable. A type declaration associates an identifier with a type. In the case of structured types (arrays and records) it also defines the structure of variables of this type. A structured type cannot contain itself.
  192. TypeDeclaration     = IdentDef "=" Type.
  193. Type     = Qualident | ArrayType | RecordType | PointerType | ProcedureType.
  194. Examples:
  195. Table = ARRAY N OF REAL
  196. Tree = POINTER TO Node
  197. Node =  RECORD
  198.     key : INTEGER;
  199.     left, right: Tree
  200. CenterTree = POINTER TO CenterNode
  201. CenterNode = RECORD (Node)
  202.     width: INTEGER;
  203.     subnode: Tree
  204. Function = PROCEDURE(x: INTEGER): INTEGER
  205. 6.1 Basic types
  206. The basic types are denoted by predeclared identifiers. The associated operators are defined in 8.2 and the predeclared function procedures in 10.3. The values of the given basic types are the following:
  207. 1.    BOOLEAN    the truth values TRUE and FALSE
  208. 2.    CHAR    the characters of the extended ASCII set (0X .. 0FFX)
  209. 3.    SHORTINT    the integers between MIN(SHORTINT) and MAX(SHORTINT)
  210. 4.    INTEGER    the integers between MIN(INTEGER) and MAX(INTEGER)
  211. 5.    LONGINT    the integers between MIN(LONGINT) and MAX(LONGINT)
  212. 6.    REAL    the real numbers between MIN(REAL) and MAX(REAL)
  213. 7.    LONGREAL    the real numbers between MIN(LONGREAL) and MAX(LONGREAL)
  214. 8.    SET    the sets of integers between 0 and MAX(SET)
  215. Types 3 to 5 are integer types, types 6 and 7 are real types, and together they are called numeric types. They form a hierarchy; the larger type includes (the values of) the smaller type:
  216.     LONGREAL  >=  REAL  >=  LONGINT  >=  INTEGER  >=  SHORTINT
  217. 6.2 Array types
  218. An array is a structure consisting of a number of elements which are all of the same type, called the element type. The number of elements of an array is called its length. The elements of the array are designated by indices, which are integers between 0 and the length minus 1.
  219. ArrayType     = ARRAY [Length {"," Length}] OF Type.
  220. Length     = ConstExpression.
  221. A type of the form
  222.     ARRAY L0, L1, ..., Ln OF T
  223. is understood as an abbreviation of
  224.     ARRAY L0 OF
  225.         ARRAY L1 OF
  226.         ...
  227.             ARRAY Ln OF T
  228. Arrays declared without length are called open arrays. They are restricted to pointer base types (see 6.4), element types of open array types, and formal parameter types (see 10.1). Examples:
  229.     ARRAY 10, N OF INTEGER
  230.     ARRAY OF CHAR
  231. 6.3 Record types
  232. A record type is a structure consisting of a fixed number of elements, called fields, with possibly different types. The record type declaration specifies the name and type of each field. The scope of the field identifiers extends from the point of their declaration to the end of the record type, but they are also visible within designators referring to elements of record variables (see 8.1). If a record type is exported, field identifiers that are to be visible outside the declaring module must be marked. They are called public fields; unmarked elements are called private fields.
  233. RecordType     = RECORD ["("BaseType")"] FieldList {";" FieldList} END.
  234. BaseType     = Qualident.
  235. FieldList     = [IdentList ":" Type ].
  236. Record types are extensible, i.e. a record type can be declared as an extension of another record type. In the example
  237.     T0 = RECORD x: INTEGER END
  238.     T1 = RECORD (T0) y: REAL END
  239. T1 is a (direct) extension of T0 and T0 is the (direct) base type of T1 (see App. A). An extended type T1 consists of the fields of its base type and of the fields which are declared in T1. All identifiers declared in the extended record must be different from the identifiers declared in its base type record(s).
  240. Examples of record type declarations:
  241. RECORD
  242.     day, month, year: INTEGER
  243. RECORD
  244.     name, firstname: ARRAY 32 OF CHAR;
  245.     age: INTEGER;
  246.     salary: REAL
  247. 6.4 Pointer types
  248. Variables of a pointer type P assume as values pointers to variables of some type T. T is called the pointer base type of P and must be a record or array type. Pointer types adopt the extension relation of their pointer base types: if a type T1 is an extension of T, and P1 is of type POINTER TO T1, then P1 is also an extension of P.
  249.     PointerType = POINTER TO Type.
  250. If p is a variable of type P = POINTER TO T, a call of the predeclared procedure NEW(p) (see 10.3) allocates a variable of type T in free storage. If T is a record type or an array type with fixed length, the allocation has to be done with NEW(p); if T is an n-dimensional open array type the allocation has to be done with NEW(p, e0, ..., en-1) where T is allocated with lengths given by the expressions e0, ..., en-1. In either case a pointer to the allocated variable is assigned to p. p is of type P. The referenced  variable p^ (pronounced as p-referenced) is of type T. Any pointer variable may assume the value NIL, which points to no variable at all.
  251. 6.5 Procedure types
  252. Variables of a procedure type T have a procedure (or NIL) as value. If a procedure P is assigned to a variable of type T, the formal parameter lists (see Ch. 10.1) of P and T must match (see App. A). P must not be a predeclared or type-bound procedure nor may it be local to another procedure.
  253.     ProcedureType = PROCEDURE [FormalParameters].
  254. 7. Variable declarations
  255. Variable declarations introduce variables by defining an identifier and a data type for them.
  256.     VariableDeclaration = IdentList ":" Type.
  257. Record and pointer variables have both a static type (the type with which they are declared - simply called their type) and a dynamic type (the type of their value at run time). For pointers and variable parameters of record type the dynamic type may be an extension of their static type. The static type determines which fields of a record are accessible. The dynamic type is used to call type-bound procedures (see 10.2).
  258. Examples of variable declarations (refer to examples in Ch. 6):
  259. i, j, k: INTEGER
  260. x, y: REAL
  261. p, q: BOOLEAN
  262. s: SET
  263. F: Function
  264. a: ARRAY 100 OF REAL
  265. w: ARRAY 16 OF RECORD
  266.         name: ARRAY 32 OF CHAR;
  267.         count: INTEGER
  268. t, c: Tree
  269. 8. Expressions
  270. Expressions are constructs denoting rules of computation whereby constants and current values of variables are combined to compute other values by the application of operators and function procedures. Expressions consist of operands and operators. Parentheses may be used to express specific associations of operators and operands.
  271. 8.1 Operands
  272. With the exception of set constructors and literal constants (numbers, character constants, or strings), operands are denoted by designators. A designator consists of an identifier referring to a constant, variable, or procedure. This identifier may possibly be qualified by a module identifier (see Ch. 4 and 11) and may be followed by selectors if the designated object is an element of a structure.
  273. Designator     = Qualident {"." ident | "[" ExpressionList "]" | "^" | "(" Qualident ")"}.
  274. ExpressionList     = Expression {"," Expression}.
  275. If a designates an array, then a[e] denotes that element of a whose index is the current value of the expression e. The type of e must be an integer type. A designator of the form a[e0, e1, ..., en] stands for a[e0][e1]...[en]. If r designates a record, then r.f denotes the field f of r or the procedure f bound to the dynamic type of r (Ch. 10.2). If p designates a pointer, p^ denotes the variable which is referenced by p. The designators p^.f and p^[e] may be abbreviated as p.f and p[e], i.e. record and array selectors imply dereferencing. If a or r are read-only, then also a[e] and r.f are read-only. 
  276.     A type guard v(T) asserts that the dynamic type of v is T (or an extension of T), i.e. program execution is aborted, if the dynamic type of v is not T (or an extension of T). Within the designator, v is then regarded as having the static type T. The guard is applicable, if
  277.     1.  v is a variable parameter of record type or v is a pointer, and if
  278.     2.  T is an extension of the static type of v
  279. If the designated object is a constant or a variable, then the designator refers to its current value. If it is a procedure, the designator refers to that procedure unless it is followed by a (possibly empty) parameter list in which case it implies an activation of that procedure and stands for the value resulting from its execution. The actual parameters must correspond to the formal parameters as in proper procedure calls (see 10.1).
  280. Examples of designators (refer to examples in Ch.7):
  281. i    (INTEGER)
  282. a[i]    (REAL)
  283. w[3].name[i]    (CHAR)
  284. t.left.right    (Tree)
  285. t(CenterTree).subnode    (Tree)
  286. 8.2 Operators
  287. Four classes of operators with different precedences (binding strengths) are syntactically distinguished in expressions. The operator ~ has the highest precedence, followed by multiplication operators, addition operators, and relations. Operators of the same precedence associate from left to right. For example, x-y-z stands for (x-y)-z.
  288. Expression     = SimpleExpression [Relation SimpleExpression].
  289. SimpleExpression    = ["+" | "-"] Term {AddOperator Term}.
  290. Term     = Factor {MulOperator Factor}.
  291. Factor     = Designator [ActualParameters] | 
  292.         number | character | string | NIL | Set | "(" Expression ")" | "~" Factor.
  293. Set     = "{" [Element {"," Element}] "}".
  294. Element     = Expression [".." Expression].
  295. ActualParameters     = "(" [ExpressionList] ")".
  296. Relation     = "=" | "#" | "<" | "<=" | ">" | ">=" | IN | IS.
  297. AddOperator     = "+" | "-" | OR.
  298. MulOperator     = "*" | "/" | DIV | MOD | "&".
  299. The available operators are listed in the following tables. Some operators are applicable to operands of various types, denoting different operations. In these cases, the actual operation is identified by the type of the operands. The operands must be expression compatible with respect to the operator (see App. A).
  300. 8.2.1 Logical operators
  301. OR    logical disjunction     p OR q      "if p then TRUE, else q"
  302. &    logical conjunction     p & q      "if p then q, else FALSE"
  303. ~    negation     ~ p      "not p"
  304. These operators apply to BOOLEAN operands and yield a BOOLEAN result.
  305. 8.2.2 Arithmetic operators
  306. +    sum
  307. -    difference
  308. *    product
  309. /    real quotient
  310. DIV    integer quotient
  311. MOD    modulus
  312. The operators +, -, *, and / apply to operands of numeric types. The type of the result is the type of that operand which includes the type of the other operand, except for division (/), where the result is the smallest real type which includes both operand types. When used as monadic operators, - denotes sign inversion and + denotes the identity operation. The operators DIV and MOD apply to integer operands only. They are related by the following formulas defined for any x and positive divisors y:
  313. x = (x DIV y) * y + (x MOD y)
  314. 0 <= (x MOD y) < y
  315. Examples:
  316. x    y    x DIV y    x MOD y
  317. 5    3    1    2
  318. -5    3    -2    1
  319. 8.2.3 Set Operators
  320. +    union
  321. -    difference (x - y = x * (-y))
  322. *    intersection
  323. /    symmetric set difference (x / y = (x-y) + (y-x))
  324. Set operators apply to operands of type SET and yield a result of type SET. The monadic minus sign denotes the complement of x, i.e. -x denotes the set of integers between 0 and MAX(SET) which are not elements of x. Set operators are not associative ((a+b)-c # a+(b-c)).
  325. A set constructor defines the value of a set by listing its elements between curly brackets. The elements must be integers in the range 0..MAX(SET). A range a..b denotes all integers in the interval [a, b].
  326. 8.2.4 Relations
  327. =    equal
  328. #    unequal
  329. <    less
  330. <=    less or equal
  331. >    greater
  332. >=    greater or equal
  333. IN    set membership
  334. IS    type test
  335. Relations yield a BOOLEAN result. The relations =, #, <, <=, >, and >= apply to the numeric types, CHAR, strings, and character arrays containing 0X as a terminator. The relations = and # also apply to BOOLEAN and SET, as well as to pointer and procedure types (including the value NIL). x IN s stands for "x is an element of s". x must be of an integer type, and s of type SET. v IS T stands for "the dynamic type of v is T (or an extension of T)" and is called a type test. It is applicable if
  336. 1.  v is a variable parameter of record type or v is a pointer, and if
  337. 2.  T is an extension of the static type of v
  338. Examples of expressions (refer to examples in Ch.7):
  339. 1991    INTEGER
  340. i DIV 3    INTEGER
  341. ~p OR q    BOOLEAN
  342. (i+j) * (i-j)    INTEGER
  343. s - {8, 9, 13}    SET
  344. i + x    REAL
  345. a[i+j] * a[i-j]    REAL
  346. (0<=i) & (i<100)    BOOLEAN
  347. t.key = 0    BOOLEAN
  348. k IN {i..j-1}    BOOLEAN
  349. w[i].name <= "John"    BOOLEAN
  350. t IS CenterTree    BOOLEAN
  351. 9. Statements
  352. Statements denote actions. There are elementary and structured statements. Elementary statements are not composed of any parts that are themselves statements. They are the assignment, the procedure call, the return, and the exit statement. Structured statements are composed of parts that are themselves statements. They are used to express sequencing and conditional, selective, and repetitive execution. A statement may also be empty, in which case it denotes no action. The empty statement is included in order to relax punctuation rules in statement sequences.
  353.     Statement =
  354.         [ Assignment | ProcedureCall | IfStatement | CaseStatement | WhileStatement | RepeatStatement |
  355.         ForStatement | LoopStatement | WithStatement | EXIT | RETURN [Expression] ].
  356. 9.1 Assignments
  357. Assignments replace the current value of a variable by a new value specified by an expression. The expression must be assignment compatible with the variable (see App. A). The assignment operator is written as ":=" and pronounced as becomes.
  358.     Assignment = Designator ":=" Expression.
  359. If an expression e of type Te is assigned to a variable v of type Tv, the following happens:
  360.     1.  if Tv and Te are record types, only those fields of Te are assigned which also belong to Tv (projection); the dynamic 
  361.         type of v  must be the same as the static type of v and  is not changed by the assignment;
  362.     2.  if Tv and Te are pointer types, the dynamic type of v becomes the dynamic type of e;
  363.     3.  if Tv is ARRAY n OF CHAR and e is a string of length m<n, v[i] becomes ei for i = 0..m-1 and v[m] becomes 0X.
  364. Examples of assignments (refer to examples in Ch.7):
  365. i := 0
  366. p := i = j
  367. x := i + 1
  368. k := log2(i+j)
  369. F := log2        (* see 10.1 *)
  370. s := {2, 3, 5, 7, 11, 13}
  371. a[i] := (x+y) * (x-y)
  372. t.key := i
  373. w[i+1].name := "John"
  374. t := c
  375. 9.2 Procedure calls
  376. A procedure call activates a procedure. It may contain a list of actual parameters which replace the corresponding formal parameters defined in the procedure declaration (see Ch. 10). The correspondence is established by the positions of the parameters in the actual and formal parameter lists. There are two kinds of parameters: variable and value parameters.
  377.     If a formal parameter is a variable parameter, the corresponding actual parameter must be a designator denoting a variable. If it denotes an element of a structured variable, the component selectors are evaluated when the formal/actual parameter substitution takes place, i.e. before the execution of the procedure. If a formal parameter is a value parameter, the corresponding actual parameter must be an expression. This expression is evaluated before the procedure activation, and the resulting value is assigned to the formal parameter (see also 10.1).
  378.     ProcedureCall = Designator [ActualParameters].
  379. Examples:
  380. WriteInt(i*2+1)    (* see 10.1 *)
  381. INC(w[k].count)
  382. t.Insert("John")    (* see 11 *)
  383. 9.3 Statement sequences
  384. Statement sequences denote the sequence of actions specified by the component statements which are separated by semicolons.
  385.     StatementSequence = Statement {";" Statement}.
  386. 9.4 If statements
  387.     IfStatement = 
  388.         IF Expression THEN StatementSequence
  389.         {ELSIF Expression THEN StatementSequence}
  390.         [ELSE StatementSequence]
  391.         END.
  392. If statements specify the conditional execution of guarded statement sequences. The Boolean expression preceding a statement sequence is called its guard. The guards are evaluated in sequence of occurrence, until one evaluates to TRUE, whereafter its associated statement sequence is executed. If no guard is satisfied, the statement sequence following the symbol ELSE is executed, if there is one.
  393. Example:
  394. IF (ch >= "A") & (ch <= "Z") THEN ReadIdentifier
  395. ELSIF (ch >= "0") & (ch <= "9") THEN ReadNumber
  396. ELSIF (ch = " ' ") OR (ch = ' " ') THEN ReadString
  397. ELSE SpecialCharacter
  398. 9.5 Case statements
  399. Case statements specify the selection and execution of a statement sequence according to the value of an expression. First the case expression is evaluated, then that statement sequence is executed whose case label list contains the obtained value. The case expression must either be of an integer type that includes the types of all case labels, or both the case expression and the case labels must be of type CHAR. Case labels are constants, and no value must occur more than once. If the value of the expression does not occur as a label of any case, the statement sequence following the symbol ELSE is selected, if there is one, otherwise the program is aborted.
  400. CaseStatement     = CASE Expression OF Case {"|" Case} [ELSE StatementSequence] END.
  401. Case     = [CaseLabelList ":" StatementSequence].
  402. CaseLabelList     = CaseLabels {"," CaseLabels}.
  403. CaseLabels     = ConstExpression [".." ConstExpression].
  404. Example:
  405. CASE ch OF
  406.     "A" .. "Z": ReadIdentifier 
  407. |    "0" .. "9": ReadNumber 
  408. |    " ' ", ' " ': ReadString
  409. ELSE SpecialCharacter
  410. 9.6 While statements
  411. While statements specify the repeated execution of a statement sequence while the Boolean expression (its guard) yields TRUE. The guard is checked before every execution of the statement sequence.
  412.     WhileStatement = WHILE Expression DO StatementSequence END.
  413. Examples:
  414. WHILE i > 0 DO i := i DIV 2; k := k + 1 END
  415. WHILE (t # NIL) & (t.key # i) DO t := t.left END
  416. 9.7 Repeat statements
  417. A repeat statement specifies the repeated execution of a statement sequence until a condition specified by a Boolean expression is satisfied. The statement sequence is executed at least once.
  418.     RepeatStatement = REPEAT StatementSequence UNTIL Expression.
  419. 9.8 For statements
  420. A for statement specifies the repeated execution of a statement sequence while a progression of values is assigned to an integer variable called the control variable of the for statement.
  421.     ForStatement = FOR ident ":=" Expression TO Expression [BY ConstExpression] DO StatementSequence END.
  422. The statement
  423.     FOR v := beg TO end BY step DO statements END
  424. is equivalent to
  425. temp := end; v := beg;
  426. IF step > 0 THEN
  427.     WHILE v <= temp DO statements; v := v + step END
  428.     WHILE v >= temp DO statements; v := v + step END
  429. temp has the same type as v. step must be a nonzero constant expression. If step is not specified, it is assumed to be 1.
  430. Examples:
  431. FOR i := 0 TO 79 DO k := k + a[i] END
  432. FOR i := 79 TO 1 BY -1 DO a[i] := a[i-1] END
  433. 9.9 Loop statements
  434. A loop statement specifies the repeated execution of a statement sequence. It is terminated upon execution of an exit statement within that sequence (see 9.10).
  435.     LoopStatement = LOOP StatementSequence END.
  436. Example:
  437.     ReadInt(i);
  438.     IF i < 0 THEN EXIT END;
  439.     WriteInt(i)
  440. Loop statements are useful to express repetitions with several exit points or cases where the exit condition is in the middle of the repeated statement sequence.
  441. 9.10 Return and exit statements
  442. A return statement indicates the termination of a procedure. It is denoted by the symbol RETURN, followed by an expression if the procedure is a function procedure. The type of the expression must be assignment compatible (see App. A) with the result type specified in the procedure heading (see Ch.10).
  443.     Function procedures must be left via a return statement indicating the result value. In proper procedures, a return statement is implied by the end of the procedure body. Any explicit return statement therefore appears as an additional (probably exceptional) termination point.
  444.     An exit statement is denoted by the symbol EXIT. It specifies termination of the enclosing loop statement and continuation with the statement following that loop statement. Exit statements are contextually, although not syntactically associated with the loop statement which contains them.
  445. 9.11 With statements
  446. With statements execute a statement sequence depending on the result of a type test and apply a type guard to every occurrence of the tested variable within this statement sequence.
  447. WithStatement     = WITH Guard DO StatementSequence {"|" Guard DO StatementSequence}
  448.         [ELSE StatementSequence] END.
  449. Guard    = Qualident ":" Qualident.
  450. If v is a variable parameter of record type or a pointer variable, and if it is of a static type T0, the statement
  451.     WITH v: T1 DO S1 | v: T2 DO S2 ELSE S3 END
  452. has the following meaning: if the dynamic type of v is T1, then the statement sequence S1 is executed where v is regarded as if it had the static type T1; else if the dynamic type of v is T2, then S2 is executed where v is regarded as if it had the static type T2; else S3 is executed. T1 and T2 must be extensions of T0. If no type test is satisfied and if an else clause is missing the program is aborted.
  453. Example:
  454.     WITH t: CenterTree DO i := t.width; c := t.subnode END
  455. 10. Procedure declarations
  456. A procedure declaration consists of a procedure heading and a procedure body. The heading specifies the procedure identifier and the formal parameters. For type-bound procedures it also specifies the receiver parameter. The body contains declarations and statements. The procedure identifier is repeated at the end of the procedure declaration.
  457.     There are two kinds of procedures: proper procedures and function procedures. The latter are activated by a function designator as a constituent of an expression and yield a result that is an operand of the expression. Proper procedures are activated by a procedure call. A procedure is a function procedure if its formal parameters specify a result type. The body of a function procedure must contain a return statement which defines its result.
  458.     All constants, variables, types, and procedures declared within a procedure body are local to the procedure. Since procedures may be declared as local objects too, procedure declarations may be nested. The call of a procedure within its declaration implies recursive activation.
  459.     Objects declared in the environment of the procedure are also visible in those parts of the procedure in which they are not concealed by a locally declared object with the same name.
  460. ProcedureDeclaration    = ProcedureHeading ";" ProcedureBody ident.
  461. ProcedureHeading     = PROCEDURE [Receiver] IdentDef [FormalParameters].
  462. ProcedureBody     = DeclarationSequence [BEGIN StatementSequence] END.
  463. DeclarationSequence     = 
  464.     {CONST {ConstantDeclaration ";"} | TYPE {TypeDeclaration ";"} | VAR {VariableDeclaration ";"} }
  465.     {ProcedureDeclaration ";" | ForwardDeclaration ";"}.
  466. ForwardDeclaration     = PROCEDURE " ^ " [Receiver] IdentDef [FormalParameters].
  467. If a procedure declaration specifies a receiver parameter, the procedure is considered to be bound to a type (see 10.2). A forward declaration serves to allow forward references to a procedure whose actual declaration appears later in the text. The formal parameter lists of the forward declaration and the actual declaration must match (see App. A).
  468. 10.1 Formal parameters
  469. Formal parameters are identifiers declared in the formal parameter list of a procedure. They correspond to actual parameters specified in the procedure call. The correspondence between formal and actual parameters is established when the procedure is called. There are two kinds of parameters, value and variable parameters, indicated in the formal parameter list by the absence or presence of the keyword VAR. Value parameters are local variables to which the value of the corresponding actual parameter is assigned as an initial value. Variable parameters correspond to actual parameters that are variables, and they stand for these variables. The scope of a formal parameter extends from its declaration to the end of the procedure block in which it is declared. A function procedure without parameters must have an empty parameter list. It must be called by a function designator whose actual parameter list is empty too. The result type of a procedure can be neither a record nor an array.
  470. FormalParameters    = "(" [FPSection {";" FPSection}] ")" [":" Qualident].
  471. FPSection     = [VAR] ident {"," ident} ":" Type.
  472. Let Tf be the type of a formal parameter f (not an open array) and Ta the type of the corresponding actual parameter a. For variable parameters, Ta must be the same as Tf, or Tf must be a record type and Ta an extension of Tf. For value parameters, a must be assignment compatible with f (see App. A).
  473.     If Tf is an open array , then a must be array compatible with f (see App. A). The lengths of f are taken from a.
  474. Examples of procedure declarations:
  475. PROCEDURE ReadInt(VAR x: INTEGER);
  476.     VAR i: INTEGER; ch: CHAR;
  477. BEGIN i := 0; Read(ch);
  478.     WHILE ("0" <= ch) & (ch <= "9") DO
  479.         i := 10*i + (ORD(ch)-ORD("0")); Read(ch)
  480.     END;
  481.     x := i
  482. END ReadInt
  483. PROCEDURE WriteInt(x: INTEGER); (*0 <= x <100000*)
  484.     VAR i: INTEGER; buf: ARRAY 5 OF INTEGER;
  485. BEGIN i := 0;
  486.     REPEAT buf[i] := x MOD 10; x := x DIV 10; INC(i) UNTIL x = 0;
  487.     REPEAT DEC(i); Write(CHR(buf[i] + ORD("0"))) UNTIL i = 0
  488. END WriteInt
  489. PROCEDURE WriteString(s: ARRAY OF CHAR);
  490.     VAR i: INTEGER;
  491. BEGIN i := 0;
  492.     WHILE (i < LEN(s)) & (s[i] # 0X) DO Write(s[i]); INC(i) END
  493. END WriteString;
  494. PROCEDURE log2(x: INTEGER): INTEGER;
  495.     VAR y: INTEGER; (*assume x>0*)
  496. BEGIN
  497.     y := 0; WHILE x > 1 DO x := x DIV 2; INC(y) END;
  498.     RETURN y
  499. END log2
  500. 10.2 Type-bound procedures
  501. Globally declared procedures may be associated with a record type declared in the same module. The procedures are said to be bound to the record type. The binding is expressed by the type of the receiver in the heading of a procedure declaration.  The receiver may be either a variable parameter of record type T or a value parameter of type POINTER TO T (where T is a record type). The procedure is bound to the type T and is considered local to it.
  502. ProcedureHeading    = PROCEDURE [Receiver] IdentDef [FormalParameters].
  503. Receiver     = "(" [VAR] ident ":" ident ")".
  504. If a procedure P is bound to a type T0, it is implicitly also bound to any type T1 which is an extension of T0. However, a procedure P' (with the same name as P) may be explicitly bound to T1 in which case it overrides the binding of P. P' is considered a redefinition of P for T1. The formal parameters of P and P' must match (see App. A). If P and T1 are exported (see Chapter 4) P' must be exported too.
  505.     If v is a designator and P is a type-bound procedure, then v.P denotes that procedure P which is bound to the dynamic type of v. Note, that this may be a different procedure than the one bound to the static type of v. v is passed to P's receiver according to the parameter passing rules specified in Chapter 10.1.
  506.     If r is a receiver parameter declared with type T, r.P^ denotes the (redefined) procedure P bound to the base type of T.
  507. In a forward declaration of a type-bound procedure the receiver parameter must be of the same type as in the actual procedure declaration. The formal parameter lists of both declarations must match (App. A).
  508. Examples:
  509. PROCEDURE (t: Tree) Insert (node: Tree);
  510.     VAR p, father: Tree;
  511. BEGIN p := t;
  512.     REPEAT father := p;
  513.         IF node.key = p.key THEN RETURN END;
  514.         IF node.key < p.key THEN p := p.left ELSE p := p.right END
  515.     UNTIL p = NIL;
  516.     IF node.key < father.key THEN father.left := node ELSE father.right := node END;
  517.     node.left := NIL; node.right := NIL
  518. END Insert;
  519. PROCEDURE (t: CenterTree) Insert (node: Tree);  (*redefinition*)
  520. BEGIN
  521.     WriteInt(node(CenterTree).width);
  522.     t.Insert^ (node)  (* calls the Insert procedure bound to Tree *)
  523. END Insert;
  524. 10.3 Predeclared procedures
  525. The following table lists the predeclared procedures. Some are generic procedures, i.e. they apply to several types of operands. v stands for a variable, x and n for expressions, and T for a type.
  526. Function procedures
  527. Name    Argument type    Result type    Function
  528. ABS(x)    numeric type    type of x    absolute value
  529. ASH(x, n)    x, n: integer type    LONGINT    arithmetic shift (x * 2n)
  530. CAP(x)    CHAR    CHAR    x is letter: corresponding capital letter
  531. CHR(x)    integer type    CHAR    character with ordinal number x
  532. ENTIER(x)    real type    LONGINT    largest integer not greater than x
  533. LEN(v, n)    v: array; n: integer const.    LONGINT    length of v in dimension n (first dimension = 0)
  534. LEN(v)    v: array    LONGINT    equivalent to LEN(v, 0)
  535. LONG(x)    SHORTINT    INTEGER    identity
  536.     INTEGER    LONGINT
  537.     REAL    LONGREAL
  538. MAX(T)    T = basic type    T    maximum value of type T
  539.     T = SET    INTEGER    maximum element of a set
  540. MIN(T)    T = basic type    T    minimum value of type T
  541.     T = SET    INTEGER    0
  542. ODD(x)    integer type    BOOLEAN    x MOD 2 = 1
  543. ORD(x)    CHAR    INTEGER    ordinal number of x
  544. SHORT(x)    LONGINT    INTEGER    identity
  545.     INTEGER    SHORTINT    identity
  546.     LONGREAL    REAL    identity (truncation possible)
  547. SIZE(T)    any type    integer type    number of bytes required by T
  548. Proper procedures
  549. Name    Argument types    Function
  550. ASSERT(x)    x: Boolean expression    terminate program execution if not x
  551. ASSERT(x, n)   x: Boolean expression; n: integer constant    terminate program execution if not x
  552. COPY(x, v)    x: character array, string; v: character array    v := x
  553. DEC(v)    integer type    v := v - 1
  554. DEC(v, n)    v, n: integer type    v := v - n
  555. EXCL(v, x)    v: SET; x: integer type    v := v - {x}
  556. HALT(n)    integer constant    terminate program execution
  557. INC(v)    integer type    v := v + 1
  558. INC(v, n)    v, n: integer type    v := v + n
  559. INCL(v, x)    v: SET; x: integer type    v := v + {x}
  560. NEW(v)    pointer to record or fixed array    allocate v ^
  561. NEW(v, x0, ..., xn) v: pointer to open array; xi: integer type    allocate v ^ with lengths x0.. xn
  562. COPY allows the assignment of a string or a character array containing a terminating 0X to another character array. If necessary, the assigned value is truncated to the target length minus one. The target will always contain 0X as a terminator. In ASSERT(x, n) and HALT(n), the interpretation of n is left to the underlying system implementation.
  563. 11. Modules
  564. A module is a collection of declarations of constants, types, variables, and procedures, together with a sequence of statements for the purpose of assigning initial values to the variables. A module constitutes a text that is compilable as a unit.
  565. Module     = MODULE ident ";" [ImportList] DeclarationSequence 
  566.         [BEGIN StatementSequence] END ident ".".
  567. ImportList     = IMPORT Import {"," Import} ";".
  568. Import     = [ident ":="] ident.
  569. The import list specifies the names of the imported modules. If a module A is imported by a module M and A exports an identifier x, then x is referred to as A.x within M. If A is imported as B := A, the object x must be referenced as B.x. This allows short alias names in qualified identifiers. A module must not import itself. Identifiers that are to be exported (i.e. that are to be visible in client modules) must be marked by an export mark in their declaration (see Chapter 4).
  570.     The statement sequence following the symbol BEGIN is executed when the module is added to a system (loaded), which is done after the imported modules have been loaded. It follows that cyclic import of modules is illegal. Individual (parameterless and exported) procedures can be activated from the system, and these procedures serve as commands (see Appendix D1).
  571. MODULE Trees;     (* exports: Tree, Node, Insert, Search, Write, Init *)
  572.     IMPORT Texts, Oberon;    (* exports read-only: Node.name *)
  573.     TYPE
  574.         Tree* = POINTER TO Node;
  575.         Node* = RECORD
  576.             name-: POINTER TO ARRAY OF CHAR;
  577.             left, right: Tree
  578.         END;
  579.     VAR w: Texts.Writer;
  580.     PROCEDURE (t: Tree) Insert* (name: ARRAY OF CHAR);
  581.         VAR p, father: Tree;
  582.     BEGIN p := t;
  583.         REPEAT father := p;
  584.             IF name = p.name^ THEN RETURN END;
  585.             IF name < p.name^ THEN p := p.left ELSE p := p.right END
  586.         UNTIL p = NIL;
  587.         NEW(p); p.left := NIL; p.right := NIL; NEW(p.name, LEN(name)+1); COPY(name, p.name^);
  588.         IF name < father.name^ THEN father.left := p ELSE father.right := p END
  589.     END Insert;
  590.     PROCEDURE (t: Tree) Search* (name: ARRAY OF CHAR): Tree;
  591.         VAR p: Tree;
  592.     BEGIN p := t;
  593.         WHILE (p # NIL) & (name # p.name^) DO
  594.             IF name < p.name^ THEN p := p.left ELSE p := p.right END
  595.         END;
  596.         RETURN p
  597.     END Search;
  598.     PROCEDURE (t: Tree) Write*;
  599.     BEGIN
  600.         IF t.left # NIL THEN t.left.Write END;
  601.         Texts.WriteString(w, t.name^); Texts.WriteLn(w); Texts.Append(Oberon.Log, w.buf);
  602.         IF t.right # NIL THEN t.right.Write END
  603.     END Write;
  604.     PROCEDURE Init* (t: Tree);
  605.     BEGIN NEW(t.name, 1); t.name[0] := 0X; t.left := NIL; t.right := NIL
  606.     END Init;
  607. BEGIN Texts.OpenWriter(w)
  608. END Trees.
  609. Appendix A: Definition of terms
  610. Integer types    SHORTINT, INTEGER, LONGINT
  611. Real types    REAL, LONGREAL
  612. Numeric types    integer types, real types
  613. Same types
  614. Two variables a and b with types Ta and Tb are of the same type if
  615. 1.  Ta and Tb are both denoted by the same type identifier, or
  616. 2.  Ta is declared to equal Tb in a type declaration of the form Ta = Tb, or
  617. 3.  a and b appear in the same identifier list in a variable, record field, or formal parameter declaration
  618.     and are not open arrays.
  619. Equal types
  620. Two types Ta and Tb are equal if
  621. 1.  Ta and Tb are the same type,  or
  622. 2.  Ta and Tb are open array types with equal element types, or
  623. 3.  Ta and Tb are procedure types whose formal parameter lists match.
  624. Type inclusion
  625. Numeric types include (the values of) smaller numeric types according to the following hierarchy:
  626.     LONGREAL >= REAL >= LONGINT >= INTEGER >= SHORTINT
  627. Type extension (base type)
  628. Given a type declaration Tb = RECORD (Ta) ... END, Tb is a direct extension of Ta, and Ta is a direct base type of Tb. A type Tb is an extension of a type Ta (Ta is a base type of Tb) if
  629. 1.  Ta and Tb are the same types, or
  630. 2.  Tb is a direct extension of an extension of Ta
  631. If Pa = POINTER TO Ta and Pb = POINTER TO Tb, Pb is an extension of Pa (Pa is a base type of Pb) if Tb is an extension of Ta.
  632. Assignment compatible
  633. An expression e of type Te is assignment compatible with a variable v of type Tv if one of the following conditions hold:
  634. 1.  Te and Tv are the same type;
  635. 2.  Te and Tv are numeric types and Tv includes Te;
  636. 3.  Te and Tv are record types and Te is an extension of Tv and the dynamic type of v is Tv ;
  637. 4.  Te and Tv are pointer types and Te is an extension of Tv;
  638. 5.  Tv is a pointer or a procedure type and e is NIL;
  639. 6.  Tv is ARRAY n OF CHAR, e is a string constant with m characters, and m < n;
  640. 7.  Tv is a procedure type and e is the name of a procedure whose formal parameters match those of Tv.
  641. Array compatible
  642. An actual parameter a of type Ta is array compatible with a formal parameter f of type Tf if
  643. 1.  Tf and Ta are the same type, or
  644. 2.  Tf is an open array, Ta is any array, and their element types are array compatible, or
  645. 3.  f is a value parameter of type ARRAY OF CHAR and a is a string.
  646. Expression compatible
  647. For a given operator, the types of its operands are expression compatible if they conform to the following table (which shows also the result type of the expression). Character arrays that are to be compared must contain 0X as a terminator. Type T1 must be an extension of type T0:
  648. operator     first operand    second operand     result type
  649. + - *    numeric    numeric    smallest numeric type including both operands
  650. /    numeric    numeric    smallest real type including both operands
  651. + - * /    SET    SET    SET
  652. DIV MOD    integer    integer    smallest integer type including both operands
  653. OR & ~    BOOLEAN    BOOLEAN    BOOLEAN
  654. = # < <= > >=    numeric    numeric    BOOLEAN
  655.     CHAR    CHAR    BOOLEAN
  656.     character array, string    character array, string    BOOLEAN
  657. = #    BOOLEAN    BOOLEAN    BOOLEAN
  658.     SET    SET    BOOLEAN
  659.     NIL, pointer type T0 or T1    NIL, pointer type T0 or T1    BOOLEAN
  660.     procedure type T, NIL    procedure type T, NIL    BOOLEAN
  661. IN    integer    SET    BOOLEAN
  662. IS    type T0    type T1    BOOLEAN
  663. Matching formal parameter lists
  664. Two formal parameter lists match if
  665. 1.  they have the same number of parameters, and
  666. 2.  they have either the same function result type or none, and
  667. 3.  parameters at corresponding positions have equal types, and
  668. 4.  parameters at corresponding positions are both either value or variable parameters.
  669. Appendix B: Syntax of Oberon-2
  670. Module     =     MODULE ident ";" [ImportList] DeclSeq  [BEGIN StatementSeq] END ident ".".
  671. ImportList     =     IMPORT [ident ":="] ident {"," [ident ":="] ident} ";".
  672. DeclSeq     =     { CONST {ConstDecl ";" } | TYPE {TypeDecl ";"} | VAR {VarDecl ";"}} {ProcDecl ";" | ForwardDecl ";"}.
  673. ConstDecl    =     IdentDef "=" ConstExpr.
  674. TypeDecl    =     IdentDef "=" Type.
  675. VarDecl    =     IdentList ":" Type.
  676. ProcDecl     =     PROCEDURE [Receiver] IdentDef [FormalPars] ";" DeclSeq [BEGIN StatementSeq] END ident.
  677. ForwardDecl    =     PROCEDURE "^" [Receiver] IdentDef [FormalPars].
  678. FormalPars     =     "(" [FPSection {";" FPSection}] ")" [":" Qualident].
  679. FPSection     =     [VAR] ident {"," ident} ":" Type.
  680. Receiver    =     "(" [VAR] ident ":" ident ")".
  681. Type     =     Qualident
  682.     |     ARRAY [ConstExpr {"," ConstExpr}] OF Type 
  683.     |     RECORD ["("Qualident")"] FieldList {";" FieldList} END
  684.     |     POINTER TO Type
  685.     |     PROCEDURE [FormalPars].
  686. FieldList     =     [IdentList ":" Type].
  687. StatementSeq    =     Statement {";" Statement}.
  688. Statement     =    [  Designator ":=" Expr 
  689.     |      Designator ["(" [ExprList] ")"] 
  690.     |      IF Expr THEN StatementSeq {ELSIF Expr THEN StatementSeq} [ELSE StatementSeq] END 
  691.     |      CASE Expr OF Case {"|" Case} [ELSE StatementSeq] END 
  692.     |      WHILE Expr DO StatementSeq END 
  693.     |      REPEAT StatementSeq UNTIL Expr 
  694.     |      FOR ident ":=" Expr TO Expr [BY ConstExpr] DO StatementSeq END 
  695.     |      LOOP StatementSeq END
  696.     |      WITH Guard DO StatementSeq {"|" Guard DO StatementSeq} [ELSE StatementSeq] END
  697.     |      EXIT 
  698.     |      RETURN [Expr]
  699.           ].
  700. Case     =     [CaseLabels {"," CaseLabels} ":" StatementSeq].
  701. CaseLabels     =     ConstExpr [".." ConstExpr].
  702. Guard    =     Qualident ":" Qualident.
  703. ConstExpr    =     Expr.
  704. Expr     =     SimpleExpr [Relation SimpleExpr].
  705. SimpleExpr    =     ["+" | "-"] Term {AddOp Term}.
  706. Term     =     Factor {MulOp Factor}.
  707. Factor     =     Designator ["(" [ExprList] ")"] | number | character | string | NIL | Set | "(" Expr ")" | " ~ " Factor.
  708. Set    =     "{" [Element {"," Element}] "}".
  709. Element     =     Expr [".." Expr].
  710. Relation     =     "=" | "#" | "<" | "<=" | ">" | ">=" | IN | IS.
  711. AddOp     =     "+" | "-" | OR.
  712. MulOp     =     " * " | "/" | DIV | MOD | "&".
  713. Designator     =     Qualident {"." ident | "[" ExprList "]" | " ^ " | "(" Qualident ")"}.
  714. ExprList     =     Expr {"," Expr}.
  715. IdentList     =     IdentDef {"," IdentDef}.
  716. Qualident     =     [ident "."] ident.
  717. IdentDef     =     ident [" * " | "-"].
  718. Appendix C: The module SYSTEM
  719. The module SYSTEM contains certain types and procedures that are necessary to implement low-level operations particular to a given computer and/or implementation. These include for example facilities for accessing devices that are controlled by the computer, and facilities to break the type compatibility rules otherwise imposed by the language definition. It is strongly recommended to restrict their use to specific modules (called low-level modules). Such modules are inherently non-portable, but easily recognized due to the identifier SYSTEM appearing in their import list. The following specifications hold for the implementation of Oberon-2 on the Ceres computer.
  720.     Module SYSTEM exports a type BYTE with the following characteristics: Variables of type CHAR or SHORTINT can be assigned to variables of type BYTE. If a formal variable parameter is of type ARRAY OF BYTE then the corresponding actual parameter may be of any type.
  721.     Another type exported by module SYSTEM is the type PTR. Variables of any pointer type may be assigned to variables of type PTR. If a formal variable parameter is of type PTR, the actual parameter may be of any pointer type.
  722.     The procedures contained in module SYSTEM are listed in the following tables. Most of them correspond to single instructions compiled as in-line code. For details, the reader is referred to the processor manual. v stands for a variable, x, y, a, and n for expressions, and T for a type.
  723. Function procedures
  724. Name    Argument types    Result type    Function
  725. ADR(v)    any    LONGINT    address of variable v
  726. BIT(a, n)    a: LONGINT    BOOLEAN    bit n of Mem[a]
  727.     n: integer
  728. CC(n)    integer constant    BOOLEAN    condition n (0 <= n <= 15)
  729. LSH(x, n)    x: integer, CHAR, BYTE    type of x    logical shift
  730.     n: integer
  731. ROT(x, n)    x: integer, CHAR, BYTE    type of x    rotation
  732.     n: integer
  733. VAL(T, x)    T, x: any type    T    x interpreted as of type T
  734. Proper procedures
  735. Name    Argument types    Function
  736. GET(a, v)    a: LONGINT; v: any basic type,    v := Mem[a]
  737.     pointer, procedure type
  738. PUT(a, x)    a: LONGINT; x: any basic type,    Mem[a] := x
  739.     pointer, procedure type
  740. GETREG(n, v)    n: integer constant; v: any basic type,    v := Register n
  741.     pointer, procedure type
  742. PUTREG(n, x)    n: integer constant; x: any basic type,    Register n := x
  743.     pointer, procedure type
  744. MOVE(a0, a1, n)    a0, a1: LONGINT; n: integer    Mem[a1.. a1+n-1] := Mem[a0.. a0+n-1]
  745. NEW(v, n)    v: any pointer; n: integer    allocate storage block of n bytes
  746.         assign its address to v
  747. Appendix D: The Oberon Environment
  748. Oberon-2 programs usually run in an environment that provides command activation, garbage collection, dynamic loading of modules, and certain run time data structures. Although not part of the language, this environment contributes to the power of Oberon-2 and is to some degree implied by the language definition. Appendix D describes the essential features of a typical Oberon environment and provides implementation hints. More details can be found in [1], [2], and [3].
  749. D1. Commands
  750. A command is any parameterless procedure P that is exported from a module M. It is denoted by M.P and can be activated under this name from the shell of the operating system. In Oberon, a user invokes commands instead of programs or modules. This gives him a finer grain of control and allows modules with multiple entry points. When a command M.P is invoked, the module M is dynamically loaded unless it is already in memory (see D2) and the procedure P is executed. When P terminates, M remains loaded. All global variables and data structures that can be reached from global pointer variables in M retain their values. When P (or another command of M) is invoked again, it may continue to use these values.
  751.     The following module demonstrates the use of commands. It implements an abstract data structure Counter that encapsulates a counter variable and provides commands to increment and print its value.
  752. MODULE Counter;
  753.     IMPORT Texts, Oberon;
  754.         counter: LONGINT;
  755.         w: Texts.Writer;
  756.     PROCEDURE Add*;   (* takes a numeric argument from the command line *)
  757.         VAR s: Texts.Scanner;
  758.     BEGIN 
  759.         Texts.OpenScanner(s, Oberon.Par.text, Oberon.Par.pos);
  760.         Texts.Scan(s);
  761.         IF s.class = Texts.Int THEN INC(counter, s.i) END
  762.     END Add;
  763.     PROCEDURE Write*;
  764.     BEGIN
  765.         Texts.WriteInt(w, counter, 5); Texts.WriteLn(w);
  766.         Texts.Append(Oberon.Log, w.buf)
  767.     END Write;
  768. BEGIN counter := 0; Texts.OpenWriter(w)
  769. END Counter.
  770. The user may execute the following two commands:
  771. Counter.Add   n     adds the value n to the variable counter
  772. Counter.Write     writes the current value of counter to the screen
  773. Since commands are parameterless they have to get their arguments from the operating system. In general, commands are free to take arguments from everywhere (e.g. from the text following the command, from the most recent selection, or from a marked viewer). The command Add uses a scanner (a data type provided by the Oberon system) to read the value that follows it on the command line.
  774.     When Counter.Add is invoked for the first time, the module Counter is loaded and its body is executed. Every call of Counter.Add n increments the variable counter by n. Every call of Counter.Write writes the current value of counter to the screen.
  775.     Since a module remains loaded after the execution of its commands, there must be an explicit way to unload it (e.g. when the user wants to substitute the loaded version by a recompiled version.) The Oberon system provides a command to do that.
  776. D2. Dynamic Loading of Modules
  777. A loaded module may invoke a command of a still unloaded module by specifying its name as a string. The specified module is then dynamically loaded and the designated command is executed. Dynamic loading allows the user to start a program as a small set of basic modules and to extend it by adding further modules at run time as the need becomes evident.
  778.     A module M0 may cause the dynamic loading of a module M1 without importing it. M1 may of course import and use M0, but M0 need not know about the existence of M1. M1 can be a module that is designed and implemented long after M0.
  779. D3. Garbage Collection
  780. In Oberon-2, the predeclared procedure NEW is used to allocate data blocks in free memory. There is, however, no way to explicitly dispose an allocated block. Rather, the Oberon environment uses a garbage collector to find the blocks that are not used any more and to make them available for allocation again. A block is in use as long as it can be reached from a global pointer variable via a pointer chain. Cutting this chain (e.g., setting a pointer to NIL) makes the block collectable. 
  781.     A garbage collector frees a programmer from the non-trivial task of deallocating data structures correctly and thus helps to avoid errors. However, it requires information about dynamic data at run time (see D5).
  782. D4. Browser
  783. The interface of a module (the declaration of the exported objects) is extracted from the module by a so-called browser which is a separate tool of the Oberon environment. For example, the browser produces the following interface of the module Trees from Ch. 11.
  784. DEFINITION Trees; 
  785.     TYPE
  786.         Tree = POINTER TO Node;
  787.         Node = RECORD
  788.             name: POINTER TO ARRAY OF CHAR;
  789.             PROCEDURE (t: Tree) Insert (name: ARRAY OF CHAR);
  790.             PROCEDURE (t: Tree) Search (name: ARRAY OF CHAR): Tree;
  791.             PROCEDURE (t: Tree) Write;
  792.         END;
  793.     PROCEDURE Init (VAR t: Tree);
  794. END Trees.
  795. For a record type, the browser also collects all procedures bound to this type and shows their declaration in the record type declaration. 
  796. D5. Run Time Data Structures
  797. Certain information about records has to be available at run time: The dynamic type of records is needed for type tests and type guards. A table with the addresses of the procedures bound to a record is needed for calling them. Finally, the garbage collector needs information about the location of pointers in dynamically allocated records. All that information is stored in so-called type descriptors of which there is one for every record type at run time. The following paragraphs show a possible implementation of type descriptors.
  798.     The dynamic type of a record corresponds to the address of its type descriptor. For dynamically allocated records this address is stored in a so-called type tag which precedes the actual record data and which is invisible for the programmer. If t is a variable of type CenterTree (see example in Ch. 6) Figure D5.1 shows one possible implementation of the run time data structures.
  799. Fig. D5.1  A variable t of type CenterTree, the record t^ it points to, and its type descriptor
  800. Since both the table of procedure addresses and the table of pointer offsets must have a fixed offset from the type descriptor address, and since both may grow when the type is extended and further procedures and pointers are added, the tables are located at the opposite ends of the type descriptor and grow in different directions.
  801.     A type-bound procedure t.P is called as t^.tag^.ProcTab[IndexP]. The procedure table index of every type-bound procedure is known at compile time. A type test v IS T is translated into v^.tag^.BaseTypes[ExtensionLevelT] = TypeDescrAdrT. Both the extension level of a record type and the address of its type descriptor are known at compile time. For example, the extension level of Node is 0 (it has no base type), and the extension level of CenterNode is 1.
  802. [1]  N.Wirth, J.Gutknecht: The Oberon System. Software Practice and Experience 19, 9, Sept. 1989
  803. [2]  M.Reiser: The Oberon System. User Guide and Programming Manual. Addison-Wesley, 1991
  804. [3]  C.Pfister, B.Heeb, J.Templ: Oberon Technical Notes. Report 156, ETH Z
  805. rich, March 1991
  806. Edit.Print lp *\m b 200 150 1650 2500 \p n ~
  807.